home *** CD-ROM | disk | FTP | other *** search
/ Power Programmierung / Power-Programmierung (Tewi)(1994).iso / magazine / aijournl / 1986_12 / aiapp.dec next >
Text File  |  1986-12-09  |  27KB  |  913 lines

  1.  
  2.                          Code Taken from
  3.                      'AI Apprentice' column
  4.               AI EXPERT magazine -- Dec. 1986 issue
  5.  
  6.  
  7.                            GRAMMAR.PAS
  8.  
  9.  
  10. {$R+}
  11. PROGRAM grammar ;
  12.  
  13. (* Copyright 1986 - MicroExpert Systems
  14.                     Box 430 R.D. 2
  15.                     Nassau, NY 12123       *)
  16.  
  17. (* GRAMMAR implements the parser described in the December 1986 AI Apprentice
  18.    column in AI Expert magazine.
  19.  
  20.    This program has been tested using Turbo ver 3.01A on an IBM PC. It has
  21.    been run under both DOS 2.1 and Concurrent 4.1 .
  22.  
  23.    To change the vocabulary that the program recognizes, change the constant
  24.    declarations in the procedures noun, verb etc. To change the grammar,
  25.    write down the new rewrite rules and code a new procedure for each one.
  26.  
  27.    We would be pleased to hear your comments, good or bad, or any applications
  28.    and modifications of the program. Contact us at the above address or
  29.    on Compuserve or BIX. Our Compuserve id is 76703,4324 and may be reached by
  30.    Easyplex mail or in the AI Expert forum. Our BIX id is bbt and we may be
  31.    contacted by BIX mail or by leaving  comments in the MicroExpert conference.
  32.  
  33.    Bill and Bev Thompson    *)
  34.  
  35.  CONST
  36.   tab = ^I ;
  37.  
  38.  TYPE
  39.   string80 = string[80] ;
  40.  
  41.  VAR
  42.   line : string80 ;
  43.  
  44.  
  45.  PROCEDURE strip_leading_blanks(VAR s : string80) ;
  46.   (* generic procedure for removing leading blanks *)
  47.   BEGIN
  48.    IF length(s) > 0
  49.     THEN
  50.      IF (s[1] = ' ') OR (s[1] = tab)
  51.       THEN
  52.        BEGIN
  53.         delete(s,1,1) ;
  54.         strip_leading_blanks(s) ;
  55.        END ;
  56.   END ; (* strip_leading_blanks *)
  57.  
  58.  
  59.  FUNCTION toupper(s : string80) : string80 ;
  60.   (* Convert the string, s, to upper case *)
  61.   VAR
  62.    i : byte ;
  63.   BEGIN
  64.    IF length(s) > 0
  65.     THEN
  66.      FOR i := 1 TO length(s) DO
  67.       s[i] := upcase(s[i]) ;
  68.    toupper := s ;
  69.   END ; (* toupper *)
  70.  
  71.  
  72.  PROCEDURE sentence(word_string : string80) ;
  73.   VAR
  74.    indent : string80 ;
  75.  
  76.   PROCEDURE error(error_msg : string80) ;
  77.    (* Display an error message and halt the program. This is a sloppy way
  78.       to end the parsing procedure. It should be changed to return an error
  79.       code and exit more elagantly. *)
  80.    BEGIN
  81.     writeln ;
  82.     writeln ;
  83.     writeln('Error : ',error_msg) ;
  84.     halt ;
  85.    END ; (* error *)
  86.  
  87.   FUNCTION get_word : string80 ;
  88.    (* Returns the first word, in upper case, from word_string *)
  89.    VAR
  90.     token : string80 ;
  91.    BEGIN
  92.     token := '' ;
  93.     strip_leading_blanks(word_string) ;
  94.     WHILE (word_string <> '') AND (copy(word_string,1,1) <> ' ') DO
  95.      BEGIN
  96.       token := concat(token,copy(word_string,1,1)) ;
  97.       delete(word_string,1,1)
  98.      END ;
  99.     get_word := toupper(token) ;
  100.    END ; (* get_word *)
  101.  
  102.   PROCEDURE noun_phrase ;
  103.    (* noun_phrase ::- determiner noun | determiner adj_set noun *)
  104.    VAR
  105.     temp_word : string80 ;
  106.  
  107.    PROCEDURE determiner ;
  108.     (* Is the first word in the current sentence a determiner *)
  109.     CONST
  110.      det_list = ' THE A ' ;
  111.     VAR
  112.      det_word : string80 ;
  113.     BEGIN
  114.      det_word := get_word ;
  115.      IF pos(concat(' ',det_word,' '),det_list) = 0
  116.       THEN error(concat('Illegal determiner --- ',det_word))
  117.       ELSE writeln(indent,'Determiner : ',det_word) ;
  118.     END ; (* determiner *)
  119.  
  120.    FUNCTION adj : boolean ;
  121.     (* Look ahead at the first word, is it an adjective ?
  122.        This routine doesn't remove the word, just looks at it *)
  123.     CONST
  124.      adj_list = ' BIG RED ' ;
  125.     VAR
  126.      adj_word : string80 ;
  127.     BEGIN
  128.      adj_word := get_word ;
  129.      word_string := concat(concat(' ',adj_word),word_string) ;
  130.      IF pos(concat(' ',adj_word,' '),adj_list)  <> 0
  131.       THEN
  132.        BEGIN
  133.         adj := true ;
  134.         writeln(indent,'Adjective : ',adj_word) ;
  135.        END
  136.       ELSE adj := false ;
  137.     END ; (* adj *)
  138.  
  139.    PROCEDURE adj_set ;
  140.     (* remove the adjectives from the front of the sentence. Stop when
  141.        a word is encountered that is not an adjective *)
  142.     VAR
  143.      adj_word : string80 ;
  144.     BEGIN
  145.      IF adj
  146.       THEN
  147.        BEGIN
  148.         adj_word := get_word ;
  149.         adj_set ;
  150.        END ;
  151.     END ; (* adj_set *)
  152.  
  153.    PROCEDURE noun ;
  154.     (* Is the first word a noun *)
  155.     CONST
  156.      nouns = ' GIRL BALL TABLE ' ;
  157.     VAR
  158.      noun_word : string80 ;
  159.     BEGIN
  160.      noun_word := get_word ;
  161.      IF pos(concat(' ',noun_word,' '),nouns) = 0
  162.       THEN error(concat('Illegal noun --- ',noun_word))
  163.       ELSE writeln(indent,'Noun : ',noun_word) ;
  164.     END ; (* noun *)
  165.  
  166.    BEGIN
  167.     writeln(indent,'Noun phrase :') ;
  168.     indent := concat('  ',indent) ;
  169.     determiner ;
  170.     IF adj
  171.      THEN
  172.       BEGIN
  173.        temp_word := get_word ;
  174.        adj_set ;
  175.        noun ;
  176.       END
  177.      ELSE noun ;
  178.     delete(indent,1,2) ;
  179.    END ; (* noun_phrase *)
  180.  
  181.   PROCEDURE verb_phrase ;
  182.    (* verb_phrase ::- verb | verb noun_phrase | verb noun_phrase prep_pharse *)
  183.  
  184.    PROCEDURE verb ;
  185.     (* Does the reamining part of the sentence start with a verb ? *)
  186.     CONST
  187.      verbs = ' MOVED PUSHED ' ;
  188.     VAR
  189.      verb_word : string80 ;
  190.     BEGIN
  191.      verb_word := get_word ;
  192.      IF pos(concat(' ',verb_word,' '),verbs) = 0
  193.       THEN error(concat('Illegal verb --- ',verb_word))
  194.       ELSE writeln(indent,'Verb : ',verb_word) ;
  195.     END ; (* verb *)
  196.  
  197.    PROCEDURE prep_phrase ;
  198.     (* prep_phrase ::- preposition noun_phrase *)
  199.  
  200.     PROCEDURE preposition ;
  201.      (* Is the first word a preposition ? *)
  202.      CONST
  203.       prep_list = ' TO FROM ' ;
  204.      VAR
  205.       prep_word : string80 ;
  206.      BEGIN
  207.       prep_word := get_word ;
  208.       IF pos(concat(' ',prep_word,' '),prep_list) = 0
  209.        THEN error(concat('Illegal preposition --- ',prep_word))
  210.        ELSE writeln(indent,'Preposition : ',prep_word) ;
  211.      END ; (* preposition *)
  212.  
  213.     BEGIN
  214.      writeln(indent,'Prepositional phrase :') ;
  215.      indent := concat('  ',indent) ;
  216.      preposition ;
  217.      noun_phrase ;
  218.      delete(indent,1,2) ;
  219.     END ; (* prep_phrase *)
  220.  
  221.    BEGIN
  222.     writeln(indent,'Verb phrase :') ;
  223.     indent := concat('  ',indent) ;
  224.     verb ;
  225.     IF word_string <> ''
  226.      THEN
  227.       BEGIN
  228.        noun_phrase ;
  229.        IF word_string <> ''
  230.         THEN prep_phrase ;
  231.        IF word_string <> ''
  232.         THEN error(concat('Illegal word ---- ',word_string)) ;
  233.       END ;
  234.     delete(indent,1,2) ;
  235.    END ; (* verb_phrase *)
  236.  
  237.   BEGIN
  238.    writeln('Sentence :') ;
  239.    indent := '  ' ;
  240.    noun_phrase ;
  241.    verb_phrase ;
  242.    writeln ;
  243.    writeln('This is a legal sentence.') ;
  244.   END ; (* sentence *)
  245.  
  246.  BEGIN
  247.   clrscr ;
  248.   writeln('Grammar - Copyright [c] 1986 MicroExpert Systems') ;
  249.   writeln ;
  250.   write('Enter a sentence : ') ;
  251.   readln(line) ;
  252.   sentence(line) ;
  253.  END.
  254.  
  255.  
  256.                            GRAMMAR.PRO
  257.  
  258. /*
  259.   Copyright 1986 - MicroExpert Systems
  260.                    Box 430 R.D. 2
  261.                    Nassau, NY 12123
  262.  
  263.   This program implements the parser described in the December 1986 AI Apprentice
  264.   column in AI Expert magazine.
  265.  
  266.   The program was developed and tested using PDPROLOG 1.7f. It should
  267.   work on just about any version of PROLOG.
  268.  
  269.   To run the program, type : consult(grammar).
  270.                              go.
  271.  
  272.   To change the vocabulary that the program recognizes, change the constant
  273.   declarations in the procedures noun, verb etc. To change the grammar,
  274.   write down the new rewrite rules and code a new procedure for each one.
  275.  
  276.   We would be pleased to hear your comments, good or bad, or any applications
  277.   and modifications of the program. Contact us at the above address or
  278.   on Compuserve or BIX. Our Compuserve id is 76703,4324 and may be reached by
  279.   Easyplex mail or in the AI Expert forum. Our BIX id is bbt and we may be
  280.   contacted by BIX mail or by leaving  comments in the MicroExpert conference.
  281.  
  282.   Bill and Bev Thompson
  283.  
  284. */
  285.  
  286. go :-
  287.     print('Enter a sentence, terminated with a "."'),nl,nl,
  288.     print('See December 1986 AI Expert for the proper grammar'),nl,
  289.     print('and vocabulary'),nl,nl,
  290.     print('==> '),
  291.     read_in(SS),nl,
  292.     parse(SS),!.
  293.  
  294.  
  295. parse(S) :-
  296.     sentence(S),
  297.     nl,nl,
  298.     print('You have entered a well formed sentence.'),nl.
  299.  
  300. parse(S) :-
  301.     nl,nl,
  302.     print('This string of words is not a well formed sentence.'),nl.
  303.  
  304.  
  305. /* A sentence is a sentence if it is made up of sentence parts */
  306.  
  307. sentence(S) :-
  308.     sentence_parts(S,['.']).
  309.  
  310. /* Sentence parts are noun_phrase verb_phrase */
  311.  
  312. sentence_parts(S0,S) :-
  313.     print('Sentence : '),nl,
  314.     noun_phrase(S0,S1,"  "),!,
  315.     verb_phrase(S1,S,"  ").
  316.  
  317.  
  318. /* noun_phrase ::= determiner noun | determiner adj_set noun
  319.    the program actually treats adj_set as if it could be empty.
  320.    This is different than the Pascal and LISP versions */
  321.  
  322. noun_phrase(S0,S,Indent) :-
  323.     print_string(Indent),
  324.     print('Noun phrase : '),nl,
  325.     append("  ",Indent,Indent2),
  326.     determiner(S0,S1,Indent2),
  327.     adj_set(S1,S2,Indent2),!,
  328.     noun(S2,S,Indent2).
  329.  
  330.  
  331. /* verb_phrase ::= verb | verb noun_phrase | verb noun_phrase prep_phrase
  332.    The program breaks this down into:
  333.    verb_phrase ::= verb obj
  334.    obj ::= [] | noun_phrase modifier
  335.    modifier ::= [] | prep_phrase
  336.    This makes it easier to trap errors and avoids duplicate printing of
  337.    nonterminals on backtracking. */
  338.  
  339. verb_phrase(S0,S,Indent) :-
  340.     print_string(Indent),
  341.     print('Verb Phrase : '),nl,
  342.     append("  ",Indent,Indent2),
  343.     verb(S0,S1,Indent2),!,
  344.     obj(S1,S,Indent2).
  345.  
  346. obj(['.'],['.'],Indent).
  347.  
  348. obj(S0,S,Indent) :-
  349.     noun_phrase(S0,S1,Indent),!,
  350.     modifier(S1,S,Indent).
  351.  
  352. modifier(['.'],['.'],Indent).
  353.  
  354. modifier(S0,S,Indent) :-
  355.     prep_phrase(S0,S,Indent).
  356.  
  357.  
  358. /* adj_set := [] | adj | adj adj_set   */
  359.  
  360. adj_set(S0,S,Indent) :-
  361.    adj(S0,S1,Indent),
  362.    adj_set(S1,S,Indent).
  363.  
  364. adj_set(S0,S,Indent) :-
  365.    adj(S0,S,Indent).
  366.  
  367. adj_set(S0,S0,Indent).
  368.  
  369.  
  370. prep_phrase(S0,S,Indent) :-
  371.     print_string(Indent),
  372.     print('Prepositional phrase : '),nl,
  373.     append("  ",Indent,Indent2),
  374.     preposition(S0,S1,Indent2),
  375.     noun_phrase(S1,S,Indent2).
  376.  
  377. /* Terminal symbol definitions :
  378.    Each, except adj, has two definitions. The second signals an error
  379.    has occurred.   */
  380.  
  381. determiner([Det|S],S,Indent) :-
  382.     member(Det,[the,a]),
  383.     print_string(Indent),
  384.     print('Determiner : ',Det),nl.
  385.  
  386. determiner([Det|S],S,Indent) :-
  387.     nl,print('Error : Illegal determiner --- ',Det),nl,
  388.     fail.
  389.  
  390. adj([Adj|S],S,Indent) :-
  391.     member(Adj,[big,red]),
  392.     print_string(Indent),
  393.     print('Adjective : ',Adj),nl.
  394.  
  395. noun([Noun_word|S],S,Indent) :-
  396.     member(Noun_word,[girl,ball,table]),
  397.     print_string(Indent),
  398.     print('Noun : ',Noun_word),nl.
  399.  
  400. noun([Noun_word|S],S,Indent) :-
  401.     nl,print('Error : Illegal noun --- ',Noun_word),nl,
  402.     fail.
  403.  
  404. verb([Verb_word|S],S,Indent) :-
  405.     member(Verb_word,[moved,pushed]),
  406.     print_string(Indent),
  407.     print('Verb : ',Verb_word),nl.
  408.  
  409. verb([Verb_word|S],S,Indent) :-
  410.     nl,print('Error : Illegal verb --- ',Verb_word),nl,
  411.     fail.
  412.  
  413. preposition([P|S],S,Indent) :-
  414.     member(P,[to,from]),
  415.     print_string(Indent),
  416.     print('Preposition : ',P),nl.
  417.  
  418. preposition([P|S],S,Indent) :-
  419.     nl,print('Error : Illegal preposition --- ',P),nl,
  420.     fail.
  421.  
  422. /*  Some Utility predicates */
  423.  
  424. member(X,[X|_]).
  425.  
  426. member(X,[_|Y]) :-
  427.     member(X,Y).
  428.  
  429.  
  430. append([],L,L).
  431.  
  432. append([X|L1],L2,[X|L3]) :- append(L1,L2,L3).
  433.  
  434.  
  435. print_string([]).
  436.  
  437. print_string([H|T]) :-
  438.     put(H),print_string(T).
  439.  
  440. /* read_in - From Clocksin and Mellish */
  441.  
  442. read_in([W|Ws]) :-
  443.     get0(C),
  444.     readword(C,W,C1),
  445.     restsent(W,C1,Ws).
  446.  
  447. restsent( W,_,[]) :-
  448.     lastword(W), !.
  449.  
  450. restsent(W,C,[W1|Ws]) :-
  451.     readword(C,W1,C1),
  452.     restsent(W1,C1,Ws).
  453.  
  454. readword(C,W,C1) :-
  455.     single_character(C), !,
  456.     name(W,[C]),
  457.     get0(C1).
  458.  
  459. readword(C,W,C2) :-
  460.     in_word(C,NewC), !,
  461.     get0(C1),
  462.     restword(C1,Cs,C2),
  463.     name(W,[NewC|Cs]).
  464.  
  465. readword(C,W,C2) :-
  466.     get0(C1),
  467.     readword(C1,W,C2).
  468.  
  469. restword(C,[NewC|Cs],C2) :-
  470.      in_word(C,NewC), !,
  471.      get0(C1),
  472.      restword(C1,Cs,C2).
  473.      restword(C,[],C).
  474.  
  475. single_character(44).  /* , */
  476. single_character(59).  /* ; */
  477. single_character(58).  /* : */
  478. single_character(63).  /* ? */
  479. single_character(33).  /* ! */
  480. single_character(46).  /* . */
  481.  
  482. in_word(C,C) :- C>96, C<123.                /* a b..z */
  483. in_word(C,L) :- C>64, C<91, L is C+32.      /* A,B..Z */
  484. in_word(C,C) :- C>47, C<58.                 /* 1,2,..9 */
  485. in_word(39,39).                             /*  ' */
  486. in_word(45,45).                             /* - */
  487.  
  488. lastword( '.' ).
  489. lastword( '!' ).
  490. lastword( '?' ).
  491.  
  492.  
  493.  
  494.                           GRAMMAR1.LSP
  495.  
  496. ;  Copyright 1986 - MicroExpert Systems
  497. ;                   Box 430 R.D. 2
  498. ;                   Nassau, NY 12123
  499. ;
  500. ;  Sentence implements the parser described in the December 1986 AI Apprentice
  501. ;  column in AI Expert magazine. This is the Pascal "clone" program. It is
  502. ;  an example of some pretty poor LISP style.
  503. ;
  504. ;  The program was implemented and tested under XLISP 1.6. It should work
  505. ;  with later versions.
  506. ;
  507. ;  To change the vocabulary that the program recognizes, change the constant
  508. ;  declarations in the procedures noun, verb etc. To change the grammar,
  509. ;  write down the new rewrite rules and code a new procedure for each one.
  510. ;
  511. ;  We would be pleased to hear your comments, good or bad, or any applications
  512. ;  and modifications of the program. Contact us at the above address or
  513. ;  on Compuserve or BIX. Our Compuserve id is 76703,4324 and may be reached by
  514. ;  Easyplex mail or in the AI Expert forum. Our BIX id is bbt and we may be
  515. ;  contacted by BIX mail or by leaving  comments in the MicroExpert conference.
  516. ;
  517. ;  Bill and Bev Thompson
  518. ;
  519. (defun sentence (word-list)
  520. ;
  521.    (let ((indent "      "))
  522. ;
  523. ;    Some simple print functions
  524. ;
  525.      (defun print-with-indent (stuff)
  526.         (princ indent)
  527.         (princ stuff))
  528. ;
  529.      (defun print-line (stuff)
  530.         (print-with-indent stuff)
  531.         (terpri))
  532. ;
  533.      (defun print-with-title (title stuff)
  534.         (print-with-indent title)
  535.         (princ " ")
  536.         (princ stuff)
  537.         (terpri))
  538. ;
  539. ;    The error function. It uses the XLISP primitive "error"
  540. ;    to terminate the program
  541. ;
  542.      (defun parse-error (message error-word)
  543.         (terpri)
  544.         (terpri)
  545.         (terpri)
  546.         (error (strcat message " --- " (symbol-name error-word))))
  547. ;
  548. ;    Extract the first word from "word-list"
  549. ;
  550.      (defun get-word ()
  551.         (let ((token (car word-list)))
  552.           (setq word-list (cdr word-list))
  553.           token))
  554. ;
  555.      (defun noun-phrase ()
  556. ;
  557.         (defun determiner ()
  558.            (let ((det-list '(a the))
  559.                  (det-word (get-word)))
  560.              (cond ((member det-word det-list)
  561.                        (print-with-title "Determiner : " det-word))
  562.                    (T (parse-error "Illegal determiner" det-word)))))
  563. ;
  564.         (defun adj ()
  565.            (let ((adj-list '(big red))
  566.                  (adj-word (get-word)))
  567.              (setq word-list (cons adj-word word-list))
  568.              (cond ((member adj-word adj-list)
  569.                       (print-with-title "Adjective : " adj-word) T)
  570.                    (T nil))))
  571. ;
  572.         (defun adj-set ()
  573.            (cond ((adj) (get-word) (adj-set))))
  574. ;
  575.         (defun noun ()
  576.             (let ((nouns '(girl ball table))
  577.                   (noun-word (get-word)))
  578.             (cond ((member noun-word nouns)
  579.                       (print-with-title "Noun : " noun-word))
  580.                   (T (parse-error "Illegal noun" noun-word)))))
  581. ;
  582.         (print-line "Noun phrase : ")
  583.         (setq indent (strcat "  " indent))
  584.         (determiner)
  585.         (cond ((adj) (get-word)
  586.                      (adj-set)
  587.                      (noun))
  588.               (T (noun)))
  589.         (setq indent (substr indent 3)))
  590. ;
  591. ;
  592.      (defun verb-phrase ()
  593. ;
  594.         (defun verb ()
  595.            (let ((verbs '(moved pushed))
  596.                  (verb-word (get-word)))
  597.            (cond ((member verb-word verbs)
  598.                      (print-with-title "Verb : " verb-word))
  599.                  (T (prase-error "Illegal verb" verb-word)))))
  600. ;
  601.         (defun prep-phrase ()
  602. ;
  603.            (defun preposition ()
  604.               (let ((prep-list '(to from))
  605.                     (prep-word (get-word)))
  606.               (cond ((member prep-word prep-list)
  607.                           (print-with-title "Preposition : " prep-word))
  608.                     (T (parse-error "Illegal preposition" prep-word)))))
  609. ;
  610.            (print-line "Prepositional phrase : ")
  611.            (setq indent (strcat "  " indent))
  612.            (preposition)
  613.            (noun-phrase)
  614.            (setq indent (substr indent 3)))
  615. ;
  616.         (print-line "Verb phrase : ")
  617.         (setq indent (strcat "  " indent))
  618.         (verb)
  619.         (cond ((not (null word-list)) (noun-phrase)
  620.                                       (cond ((not (null word-list))
  621.                                                (prep-phrase)))))
  622.         (setq indent (substr indent 3)))
  623. ;
  624. ;
  625.      (print-line "Sentence : ")
  626.      (setq indent (strcat "  " indent))
  627.      (noun-phrase)
  628.      (verb-phrase)
  629.      (terpri)
  630.      (terpri)
  631.      (terpri)
  632.      (print "You have entered a legal sentence")
  633.      NIL))
  634. ;
  635. ;
  636. ;   Opening instructions
  637. ;
  638. (terpri)
  639. (princ "To run the parser, Type: (sentence '(the girl moved the ball))")
  640. (terpri)
  641. (terpri)
  642. (princ "See December 1986 AI Expert magazine for a description of")
  643. (terpri)
  644. (princ "the grammar that this routine implements.")
  645. (terpri)
  646. (terpri)
  647.  
  648.  
  649.                           GRAMMAR2.LSP
  650.  
  651.  
  652. ;  Copyright 1986 - MicroExpert Systems
  653. ;                   Box 430 R.D. 2
  654. ;                   Nassau, NY 12123
  655. ;
  656. ;  Sentence implements the parser described in the December 1986 AI Apprentice
  657. ;  column in AI Expert magazine. This is the Pascal "clone" program. This is
  658. ;  the slightl more LISP-like version. It could also stand some improvement.
  659. ;  For example,most of the local varaibles are unnecessary.
  660. ;
  661. ;  The program was implemented and tested under XLISP 1.6. It should work
  662. ;  with later versions.
  663. ;
  664. ;  To change the vocabulary that the program recognizes, change the constant
  665. ;  declarations in the procedures noun, verb etc. To change the grammar,
  666. ;  write down the new rewrite rules and code a new procedure for each one.
  667. ;
  668. ;  We would be pleased to hear your comments, good or bad, or any applications
  669. ;  and modifications of the program. Contact us at the above address or
  670. ;  on Compuserve or BIX. Our Compuserve id is 76703,4324 and may be reached by
  671. ;  Easyplex mail or in the AI Expert forum. Our BIX id is bbt and we may be
  672. ;  contacted by BIX mail or by leaving  comments in the MicroExpert conference.
  673. ;
  674. ;  Bill and Bev Thompson
  675. ;
  676. (defun print-line (indent line)
  677.    (princ indent)
  678.    (princ line)
  679.    (terpri))
  680. ;
  681. ;
  682. (defun print-word (indent title word)
  683.    (princ indent)
  684.    (princ title)
  685.    (princ word)
  686.    (terpri))
  687. ;
  688. ;
  689. (defun parse-error (message error-word)
  690.    (terpri)
  691.    (terpri)
  692.    (terpri)
  693.    (error (strcat message " --- " (symbol-name error-word))))
  694. ;
  695. ;
  696. (defun determiner (word-list indent)
  697.    (let ((det-list '(a the)))
  698.       (cond ((member (car word-list) det-list)
  699.                  (print-word indent "Determiner : " (car word-list))
  700.                  (cdr word-list))
  701.              (T (parse-error "Illegal determiner " (car word-list))))))
  702. ;
  703. ;
  704. (defun adj (word-list indent)
  705.    (let ((adj-list '(big red)))
  706.      (cond ((member (car word-list) adj-list)
  707.                   (print-word indent "Adjective : " (car word-list))
  708.                   T)
  709.             (T nil))))
  710. ;
  711. ;
  712. (defun adj-set (word-list indent)
  713.    (cond ((adj word-list indent) (adj-set (cdr word-list) indent))
  714.          (T word-list)))
  715. ;
  716. ;
  717. (defun noun (word-list indent)
  718.    (let ((nouns '(girl ball table)))
  719.      (cond ((member (car word-list) nouns)
  720.                  (print-word indent "Noun : " (car word-list))
  721.                  (cdr word-list))
  722.            (T (parse-error "Illegal noun " (car word-list))))))
  723. ;
  724. ;
  725. (defun noun-phrase (word-list indent)
  726.    (let ((remaining-words nil))
  727.      (print-line indent "Noun phrase : ")
  728.      (setq remaining-words (determiner word-list (strcat "  " indent)))
  729.      (cond ((adj remaining-words (strcat "  " indent))
  730.                     (setq remaining-words (adj-set (cdr remaining-words)
  731.                                                (strcat "  " indent)))
  732.                     (noun remaining-words (strcat "  " indent)))
  733.            (T (noun remaining-words (strcat "  " indent))))))
  734. ;
  735. ;
  736. (defun verb (word-list indent)
  737.    (let ((verbs '(moved pushed)))
  738.      (cond ((member (car word-list) verbs)
  739.                  (print-word indent "Verb : " (car word-list))
  740.                  (cdr word-list))
  741.            (T (parse-error "Illegal verb " (car word-list))))))
  742. ;
  743. ;
  744. (defun preposition (word-list indent)
  745.    (let ((prep-list '(to from)))
  746.      (cond ((member (car word-list) prep-list)
  747.                  (print-word indent "Preposition : " (car word-list))
  748.                  (cdr word-list))
  749.            (T (parse-error "Illegal preposition " (car word-list))))))
  750. ;
  751. ;
  752. (defun prep-phrase (word-list indent)
  753.    (let ((remaining-words nil))
  754.      (print-line indent "Prepositional phrase :")
  755.      (setq remaining-words (preposition word-list (strcat "  " indent)))
  756.      (noun-phrase remaining-words (strcat "  " indent))))
  757. ;
  758. ;
  759. (defun verb-phrase (word-list indent)
  760.    (let ((remaining-words nil))
  761.      (print-line indent "Verb phrase :")
  762.      (setq remaining-words (verb word-list (strcat "  " indent)))
  763.      (cond ((not (null remaining-words))
  764.                 (setq remaining-words (noun-phrase remaining-words
  765.                                            (strcat "  " indent)))
  766.                 (cond ((not (null remaining-words))
  767.                            (setq remaining-words
  768.                                    (prep-phrase remaining-words
  769.                                         (strcat "  " indent)))))))))
  770. ;
  771. ;
  772. ;
  773. (defun sentence (word-list)
  774.    (let ((remaining-words nil))
  775.      (print-line "" "Sentence : ")
  776.      (setq remaining-words (noun-phrase word-list "  "))
  777.      (cond ((null (verb-phrase remaining-words "  "))
  778.                  (terpri)
  779.                  (princ "You have entered a legal sentence.")
  780.                  (terpri)
  781.                  NIL))))
  782. ;
  783. ;
  784. ;   Opening instructions
  785. ;
  786. (terpri)
  787. (princ "To run the parser, Type: (sentence '(the girl moved the ball))")
  788. (terpri)
  789. (princ "See December 1986 AI Expert magazine for a description of")
  790. (terpri)
  791. (terpri)
  792. (princ "the grammar that this routine implements.")
  793. (terpri)
  794. (terpri)
  795.  
  796.  
  797.  
  798.                  FIGURES IN THIS MONTH'S COLUMN
  799.  
  800.  
  801. sentence ::= noun_phrase verb_phrse
  802. noun_phrase ::= determiner adj_set noun | determiner noun
  803. adj_set ::= adj | adj adj_set
  804. verb_phrase ::= verb | verb noun_phrase | verb noun_pharse prep_phrase
  805. prep_phrase ::= preposition noun_phrase
  806. determiner ::= "a" | "the"
  807. noun ::= "girl" | "ball"
  808. adj ::= "big" | "red"
  809. verb ::= "moved" | "pushed"
  810. preposition ::= "to | "from"
  811.  
  812. Figure 1 - Rules for a simple context-free grammar
  813.  
  814.  
  815.  
  816. PROCEDURE sentence               |    (defun sentence (word_string)
  817.           (word_string : string) |               .
  818.  .                               |               .
  819.  .                               |            (print-line "Sentence : ")
  820.  .                               |            (setq indent "  ")
  821.  .                               |            (noun-phrase)
  822.                                  |            (verb-phrase))
  823. BEGIN                            |
  824.  writeln('Sentence : ') ;        |
  825.  indent := '  ' ;                |
  826.  noun_phrase ;                   |
  827.  verb_phrase ;                   |
  828. END ; (* sentence *)             |
  829.                                  |
  830.  
  831. Figure 2 - Pascal and LISP code to begin parsing the grammar.
  832.  
  833.  
  834.  
  835. PROCEDURE noun_phrase ;             |   (defun noun ()
  836.  .                                  |       .                 
  837.  .                                  |       .
  838.  .                                  |   (print-line indent "Noun Phrase :")
  839.  .                                  |   (setq indent (strcat "  " indent))
  840.                                     |   (determiner)
  841.  BEGIN                              |   (cond ((adj) (get-word)
  842.   writeln(indent,'Noun Phrase :') ; |                (adj-set)
  843.   indent := concat ('  ',indent) ;  |               (noun))
  844.   determiner ;                      |         (T (noun)))
  845.   IF adj                            |
  846.    THEN                             |
  847.     BEGIN                           |
  848.      temp := get_word ;             |
  849.      adj_set ;                      |
  850.      noun ;                         |
  851.     END                             |
  852.    ELSE noun ;                      |
  853.   delete (indent,1,2) ;             |
  854. END ; (* noun_phrase *)             |
  855.  
  856. Figure 3 - Pascal and LISP code for finding noun phrases.
  857.  
  858.  
  859.  
  860.  
  861. PROCEDURE determiner ;                                    | (defun determiner ()
  862.  CONST                                                    |     (let ((det-list '(a the))
  863.    det_list = ' a the ' ;                                 |           (det-word (get-word))
  864.  VAR                                                      |       (cond ((member det-word det-list)
  865.    det_word : string80 ;                                  |                 (print-line indent "Determiner : " det-word))
  866.  BEGIN                                                    |             (T (parse-error "Illegal Determiner --- " det-word)))))
  867.    det_word := get_word ;                                 |
  868.    IF pos(concat(' ',det_word,' '),det_list) = 0          |
  869.      THEN error(concat(Illegal determiner --- ',det_word))|
  870.      ELSE writeln(indent,'Determiner : ',det_word) ;      |
  871.  END ; (* determiner *)                                   |
  872.  
  873. Figure 4 - Pascal and LISP code for finding determiners.
  874.  
  875.  
  876.  
  877. Sentence :
  878.   Noun phrase :
  879.     Determiner : the
  880.     Noun : girl
  881.   Verb phrase :
  882.     Verb : moved
  883.     Noun phrase :
  884.       Determiner : the
  885.       Noun : ball
  886.     Prepositional phrase :
  887.       Preposition : to
  888.       Noun phrase :
  889.         Determiner : the
  890.         Adjective : big
  891.         Adjective : red
  892.         Noun : table
  893.  
  894. Figure 5 - The parse tree for "the girl moved the ball to the big red table"
  895.  
  896.  
  897.  
  898.  
  899. sentence
  900.      noun_phrase
  901.           determiner
  902.           adj
  903.           adj_set
  904.           noun
  905.      verb_phrase
  906.           verb
  907.           prep_phrase
  908.                preposition
  909.  
  910. Figure 6 -  The block structure of the recursive descent parser.
  911.  
  912.  
  913.